" NAME printOutInLatex AUTHOR iforwyn williams FUNCTION browser prints in LaTeX; you need st80Macros.tex ST-VERSIONS 2.2 PREREQUISITES CONFLICTS DISTRIBUTION world VERSION 1.1 DATE 22 Jan 1989 SUMMARY printOutInLatex prints things out in LaTeX. Everything is done in terms of macros in /usr/lib/tex/macros/st80Macros.tex (appended). (2.2).IWW 'This is a latex dumper for Smalltalk code. It provides a Latex-out menu option in each Browser list. Before you file it in, you may like to check that the menus here are the same as your present Browser menus, plus the Latex option. Search for \LaTeX and check the list against your own browser. The latex output expects a file st80Macros.tex, which you should have received with this. % The following contains the LaTeX macros required by the Smalltalk % pretty printing routine. Every control sequence used by the pretty % printer is a macro defined in this file % beware of the duplicated double quotes! % Minor improvements 9/8/88 alan@uk.ac.man.cs %############################################################################## %# # %# # %# This first section contains the macros for the class description headings. # %# # %# # %############################################################################## \newcommand{\tabInSource}{} % so that it may be \renewcommanded \newcommand{\eolnInSource}{\ } % so that it may be \renewcommanded \newcommand{\classSeparator}{\newpage} \newcommand{\superClass}[1]{{\small\rm superclass}\>{\normalsize\sf #1}\\} \newcommand{\instanceVariables}[1]{{\small\rm instance variables} \>{\normalsize\sf #1}\\} \newcommand{\moreInstanceVariables}[1]{\>{\normalsize\sf #1}\\} \newcommand{\classVariables}[1]{{\small\rm class variables} \>{\normalsize\sf #1}\\} \newcommand{\moreClassVariables}[1]{\>{\normalsize\sf #1}\\} \newcommand{\poolDictionaries}[1]{{\small\rm pool dictionaries} \>{\normalsize\sf #1}\\} \newcommand{\morePoolDictionaries}[1]{\>{\normalsize\sf #1}\\} \newcommand{\classCategory}[1]{{\small\rm class category} \>{\normalsize\sf #1}} \newcommand{\composeHeading}[1]{\markright{\timeHeading\ \ \ #1}} \newcommand{\methodCategory}[1]{\noindent\pagebreak[3]\newline {\Large\rm #1}} \newcommand{\comment}[1]{ ``{\em #1}\/''} \newcommand{\commentStart}{\bgroup\protect\renewcommand{\tabInSource}{\rule{2em}{0pt}}\em``} \newcommand{\commentBreak}{\\[0.5ex]} % break in long comment \newcommand{\commentEnd}{\leavevmode\/''\egroup\newline} \pagestyle{myheadings}\markright{} \newcommand{\timeHeading}{} \newcommand{\timeTitle}[1]{\renewcommand{\timeHeading}{#1}\composeHeading{}% } % Displays time and version. \newenvironment{classHeading}{\pagebreak[3]\begin{tabbing} instance variables \= \kill}{\end{tabbing}\nopagebreak} \newcommand{\class}[1]{\composeHeading{#1}% \rule{\linewidth}{.01in}\\{\small\rm class}\>{\Large\bf #1}\\} % This next env integrates functions of classHeading env and \class. \newenvironment{classHead}[1]{\composeHeading{#1}% \pagebreak[3]\begin{tabbing} instance variables \= \kill \rule{\linewidth}{.01in}\\{\small\rm class}\>{\Large\bf #1}\\ }{\end{tabbing}\nopagebreak} \newenvironment{method}[1]{\pagebreak[2]\begin{list}{}{\setlength{\leftmargin}{0.2in}}\protect\renewcommand{\tabInSource}{\ \ \ }\protect\renewcommand{\eolnInSource}{\nopagebreak[2]\newline\mbox{}}\item {\bf #1 \nopagebreak[3]\newline}\sf}{\protect\renewcommand{\tabInSource}{}\protect\renewcommand{\eolnInSource}{\newline\pagebreak}\end{list}} %############################################################################## %# # %# # %# This second section contains the macros for characters used in Smalltalk. # %# # %# # %############################################################################## \newcommand{\plusSymbol}{$+$} % + \newcommand{\minusSymbol}{$-$} % - \newcommand{\multiplySymbol}{$*$} % * \newcommand{\forwardSlash}{$/$} % / \newcommand{\reverseSlash}{$\backslash$} % \ \newcommand{\verticalBar}{$\mid$} % | \newcommand{\openSquareBracket}{$[$} % [ \newcommand{\closeSquareBracket}{$]$} % ] \newcommand{\openCurlyBracket}{$\{$} % { \newcommand{\closeCurlyBracket}{$\}$} % } \newcommand{\openBracket}{$($} % ( \newcommand{\closeBracket}{$)$} % ) \newcommand{\ampersand}{\&} % & \newcommand{\hashSymbol}{\#} % # \newcommand{\questionMark}{?} % ? \newcommand{\dollarSymbol}{\$} % $ \newcommand{\plingSymbol}{!!} % !! \newcommand{\atSymbol}{@} % @ \newcommand{\lessThan}{$<$ } % < \newcommand{\greaterThan}{$>$ } % > \newcommand{\equalsSymbol}{$=$} % = \newcommand{\singleQuote}{'} % ' \newcommand{\doubleLeftQuote}{{\tt ""}} % '' \newcommand{\leftArrow}{$\leftarrow$ } % <- \newcommand{\upArrow}{$\uparrow$} % ^ \newcommand{\tilderSymbol}{$\sim$} % ~ \newcommand{\none}{{\em none}} % 'none' 'From Smalltalk-80, version 2, of April 1, 1983 on 30 October 1986 at 8:12:24 pm'! TimeZone initializeDefaultTimeZone: 0! Cursor addClassVarName: 'TexCursor'! !ChangeSet class methodsFor: 'fileIn/Out'! superclassOrder: classes "Arrange the classes in the collection, classes, in superclass order so the classes can be properly filed in. Class A must come before class B if A is a superclass of B, or if B is A's metaclass." "SystemOrganization superclassOrder: 'System-Changes' " ( classes select: [:c| ((classes includes: c superclass) or: [(c isKindOf: Metaclass) and: [classes includes: c soleInstance]] ) not ] ) inject: OrderedCollection new into: [:list :top | list addAll: (self superclassOrder: classes under: top). list] "Fixed so as to enforce alpha ordering as far as possible ---alan"! superclassOrder: classes under: top | subs sift o | "Answer the descendant classes of top which appear in classes" subs _ SortedCollection sortBlock: [:x :y| x name <= y name]. subs addAll: top subclasses. sift _ (OrderedCollection with: top class). sift addAll: subs. o _ OrderedCollection with: top. o addAll: (sift inject: OrderedCollection new into: [:list :sub | (classes includes: sub) ifTrue: [list addAll: (self superclassOrder: classes under: sub)]. list]). ^o! ! !Cursor class methodsFor: 'class initialization'! texCursorInitialize "initialize the print out in LaTeX cursor - Cursor tex" TexCursor _ (Cursor extent: 16@16 fromArray: #( 2r0 2r0 2r0 2r111110000110011 2r101010000010010 2r1000000011110 2r1011111001100 2r1001000001100 2r1001000011110 2r1001111010010 2r11101000110011 2r1000000000 2r11111000000 2r0 2r0 2r0) offset: 0@0)! ! !Cursor class methodsFor: 'constants'! "Answer the instance of me that spells TeX." ^TexCursor! ! Cursor texCursorInitialize! !Character class methodsFor: 'accessing untypeable characters'! "Answer the Character representing a line feed." ^self value: 10! ! !WriteStream methodsFor: 'character writing'! "Append a linefeed character to the receiver." self nextPut: Character lf! ! !Browser methodsFor: 'category list'! categoryMenu "Browser flushMenus" category == nil ifTrue: [^ ActionMenu labels: 'add category\update\edit all\find class' withCRs lines: #(1 3) selectors: #(addCategory updateCategories editCategories findClass)]. CategoryMenu == nil ifTrue: [CategoryMenu _ ActionMenu labels: 'file out\LaTeX out\spawn\add category\rename\remove\update\edit all\find class' withCRs lines: #(3 6 8) selectors: #(fileOutCategory printOutCategory spawnCategory addCategory renameCategory removeCategory updateCategories editCategories findClass)]. ^ CategoryMenu! ! !Browser methodsFor: 'class list'! classMenu "Browser flushMenus" className == nil ifTrue: [^nil]. ClassMenu == nil ifTrue: [ClassMenu _ ActionMenu labels: 'file out\LaTeX out\spawn\spawn hierarchy hierarchy\definition\comment\protocols inst var refs\class var refs\class refs find method rename\remove' withCRs lines: #(4 8 11 12) selectors: #(fileOutClass printOutClass spawnClass spawnHierarchy showHierarchy editClass editComment editProtocols browseFieldReferences browseClassVariables browseClassReferences findMethodAndSelectAlphabetic renameClass removeClass)]. ^ ClassMenu! ! !Browser methodsFor: 'protocol list'! protocolMenu "Browser flushMenus" protocol == nil ifTrue: [^ ActionMenu labels: 'add protocol' selectors: #(addProtocol)]. ProtocolMenu == nil ifTrue: [ProtocolMenu _ ActionMenu labels: 'file out\LaTeX out\spawn\add protocol\rename\remove' withCRs lines: #(3) selectors: #(fileOutProtocol printOutProtocol spawnProtocol addProtocol renameProtocol removeProtocol)]. ^ ProtocolMenu! ! !Browser methodsFor: 'selector list'! selectorMenu "Browser flushMenus" selector == nil ifTrue: [^ nil]. MessageMenu == nil ifTrue: [MessageMenu _ ActionMenu labels: 'file out\LaTeX out\spawn\senders\implementors\messages\move\remove' withCRs lines: #(3 6) selectors: #(fileOutMessage printOutMessage spawnMethod browseSenders browseImplementors browseMessages moveMethod removeMethod)]. ^ MessageMenu! !Browser flushMenus! !Browser methodsFor: 'category functions'! printOutCategory SystemOrganization printOutCategory: category! ! !Browser methodsFor: 'class functions'! printOutClass self selectedClass printOutClass! ! !Browser methodsFor: 'protocol functions'! printOutProtocol self selectedClass printOutProtocol: protocol! ! !Browser methodsFor: 'selector functions'! printOutMessage |fileName | self selectedClass printOutMessage: selector! ! ClassDescription addClassVarName: 'CharacterMappingDictionary'! !ClassDescription methodsFor: 'private'! initializeLatexCharacterMappingDictionary "Initializes the LaTeX character mapping dictionary" CharacterMappingDictionary _ Dictionary new. CharacterMappingDictionary at: $% put: '\%'. CharacterMappingDictionary at: $~ put: '\tilderSymbol '. CharacterMappingDictionary at: $@ put: '\atSymbol '. CharacterMappingDictionary at: $' put: '\singleQuote '. CharacterMappingDictionary at: $" put: '\doubleLeftQuote '. CharacterMappingDictionary at: $- put: '\minusSymbol '. CharacterMappingDictionary at: $* put: '\multiplySymbol '. CharacterMappingDictionary at: $+ put: '\plusSymbol '. CharacterMappingDictionary at: $^ put: '\upArrow '. CharacterMappingDictionary at: $\ put: '\reverseSlash '. CharacterMappingDictionary at: $/ put: '\forwardSlash '. CharacterMappingDictionary at: $$ put: '\dollarSymbol '. CharacterMappingDictionary at: $!! put: '\plingSymbol '. CharacterMappingDictionary at: $| put: '\verticalBar '. CharacterMappingDictionary at: $_ put: '\leftArrow '. CharacterMappingDictionary at: $& put: '\ampersand '. CharacterMappingDictionary at: $[ put: '\openSquareBracket '. CharacterMappingDictionary at: $] put: '\closeSquareBracket '. CharacterMappingDictionary at: ${ put: '\openCurlyBracket '. CharacterMappingDictionary at: $} put: '\closeCurlyBracket '. CharacterMappingDictionary at: $( put: '\openBracket '. CharacterMappingDictionary at: $) put: '\closeBracket '. CharacterMappingDictionary at: $< put: '\lessThan '. CharacterMappingDictionary at: $> put: '\greaterThan '. CharacterMappingDictionary at: $= put: '\equalsSymbol '. CharacterMappingDictionary at: $# put: '\hashSymbol '. CharacterMappingDictionary at: $? put: '\questionMark '. CharacterMappingDictionary at: Character cr put: '\eolnInSource '. CharacterMappingDictionary at: Character tab put: '\tabInSource '. CharacterMappingDictionary at: Character space put: '\ '! ! !ClassDescription methodsFor: 'fileIn/Out'! printCategoryChunk: aString on: aFileStream "print category definition on aFileStream" aFileStream cr; cr; nextPut: $!!. aFileStream nextChunkPut: self name , ' methodsFor: ' , '''' , aString , ''''! ! !ClassDescription methodsFor: 'printOutInLatex'! printClassOn: fileStream "Create a readable version of the message category aString, and send to a printer." Cursor tex showWhile: self printOutStartUp: fileStream. self printOutTimeStamp: fileStream with: self name asString. self printOutOn: fileStream. self printOutCloseDown: fileStream. fileStream shorten; close]! printOutClass "Create a readable version of the class definition." | fileName fileStream | Cursor tex showWhile: [fileName _ FillInTheBlank request: 'LaTeX file' initialAnswer: (FileDirectory fixFileName: self name , '.tex'). fileName = '' ifFalse: [ self printClassOn: (FileStream fileNamed: fileName)]]! printMethodChunk: aSelector on: aFileStream moveSource: moveSource toFile: fileIndex "Print the source code for the method associated with the argument selector onto the fileStream. aFileStream, and, for backup, if the argument moveSource (a Boolean) is true, also set the file index within the method to be the argument fileIndex." | position | aFileStream lf. Cursor write showWhile: [moveSource ifTrue: [position _ aFileStream position. aFileStream nextChunkPut: (self sourceCodeAt: aSelector). (self compiledMethodAt: aSelector) setSourcePosition: position inFile: fileIndex] ifFalse: [aFileStream lf; nextChunkPut: (self sourceCodeAt: aSelector)]]! printOutProtocol: aString "Create a readable version of the protocol (message category) aString, and send to a printer." | fileName fileStream | Cursor tex showWhile: [fileName _ FillInTheBlank request: 'LaTeX file' initialAnswer: (FileDirectory fixFileName: (self name, '-', aString , '.tex')). fileName = '' ifFalse: [ fileStream _ FileStream fileNamed: fileName. self printOutStartUp: fileStream. self printOutTimeStamp: fileStream with: self name, ' $>$ ', aString.. self printOutDefinitionOn: fileStream. self printOutProtocol: aString on: fileStream. self printOutCloseDown: fileStream. fileStream shorten; close]]! printOutProtocol: aString on: aFileStream "File a description of the receiver's category, aString, onto aFileStream. " self printOutMacro: '\methodCategory' with: aString on: aFileStream. (self organization listAtCategoryNamed: aString) do: [:sel | self printOutMessage: sel on: aFileStream]! printOutCloseDown: fileStream fileStream nextPutAll: '\end{document} '; lf! printOutCommentOn: fileStream | comm prev numberOfCharactersOnThisLine | comm _ self comment. comm size = 0 ifTrue: [^self]. self printOutMacro: '\commentStart' with: nil on: fileStream. prev _ Character space. numberOfCharactersOnThisLine _ 0. comm do: [:this | numberOfCharactersOnThisLine _ numberOfCharactersOnThisLine + 1. (numberOfCharactersOnThisLine > 70 and: [this asInteger <= Character space asInteger]) ifTrue: [fileStream lf. numberOfCharactersOnThisLine _ 0]. ((this = Character tab) | (this = Character cr) and: [prev = Character cr]) ifTrue: [self printOutMacro: '\commentBreak' with: nil on: fileStream]. (CharacterMappingDictionary includesKey: this) ifTrue: [fileStream nextPutAll: (CharacterMappingDictionary at: this). this = Character cr ifTrue: [fileStream lf. numberOfCharactersOnThisLine _ 0]] ifFalse: [fileStream nextPut: this]. prev _ this]. fileStream lf. self printOutMacro: '\commentEnd' with: nil on: fileStream! printOutDefinitionOn: fileStream | names first sc | self printOutMacro: '\begin{classHeading}\class' with: self name on: fileStream. " printOutMacro: '\begin{classHead}{', self name, '}' with: '' on: fileStream. " sc _ self superclass. sc isNil ifTrue: [self printOutMacro: '\superClass' with: 'nil' on: fileStream] ifFalse: [self printOutMacro: '\superClass' with: sc name on: fileStream]. names _ self instVarNames. names size = 0 ifTrue: [self printOutMacro: '\instanceVariables' with: '\none' on: fileStream]. names size > 0 ifTrue: [self printOutMacro: '\instanceVariables' with: (names at: 1) on: fileStream]. names size > 1 ifTrue: [2 to: names size do: [:index | self printOutMacro: '\moreInstanceVariables' with: (names at: index) on: fileStream]]. names _ self classPool keys asSortedCollection. names size = 0 ifTrue: [self printOutMacro: '\classVariables' with: '\none' on: fileStream] ifFalse: [first _ true. names do: [:each | first ifTrue: [self printOutMacro: '\classVariables' with: each on: fileStream. first _ false] ifFalse: [self printOutMacro: '\moreClassVariables' with: each on: fileStream]]]. names _ self sharedPools. names size = 0 ifTrue: [self printOutMacro: '\poolDictionaries' with: '\none' on: fileStream] ifFalse: [first _ true. names do: [:each | first ifTrue: [self printOutMacro: '\poolDictionaries' with: (Smalltalk keyAtValue: each) on: fileStream. first _ false] ifFalse: [self printOutMacro: '\morePoolDictionaries' with: (Smalltalk keyAtValue: each) on: fileStream]]]. self category ~= nil ifTrue: [self printOutMacro: '\classCategory' with: self category on: fileStream]. self printOutMacro: '\end' with: 'classHeading' on: fileStream "self printOutMacro: '\end' with: 'classHead' on: fileStream"! printOutMacro: macroName with: argString on: aFileStream aFileStream nextPutAll: macroName. argString ~= nil ifTrue: [aFileStream nextPut: ${ ; nextPutAll: argString asString; nextPut: $} ]. aFileStream lf! printOutMessage: aString "Create a readable version of the message with selector aString, and send to a printer. Defaults to fileOut." | fileName | Cursor tex showWhile: fileName _ FillInTheBlank request: 'LaTeX out on' initialAnswer: (FileDirectory fixFileName: self name, '-', aString, '.tex'). fileName = '' ifFalse: [ self printOutMessage: aString fileName: fileName]]! printOutMessage: aString fileName: fileName | fileStream | fileStream _ FileStream fileNamed: fileName. self printOutStartUp: fileStream. self printOutTimeStamp: fileStream with: self name, ' $>>$ ', aString.. self printOutDefinitionOn: fileStream. self printOutMacro: '\methodCategory' with: 'in ', (self whichCategoryIncludesSelector: aString) on: fileStream. self printOutMessage: aString on: fileStream. self printOutCloseDown: fileStream. fileStream close! printOutMessage: aString on: aFileStream "Create LaTeX file for the method aString" | sourceCode bodyStart characterMappingDictionary numberOfCharactersOnThisLine | sourceCode _ self sourceCodeAt: aString asSymbol. bodyStart _ sourceCode findString: '\' withCRs startingAt: 1. bodyStart = 0 ifTrue: ["one liner?" bodyStart _ (sourceCode findString: '^' startingAt: 1)-1]. bodyStart > 0 ifTrue: [self printOutMacro: '\begin{method}' with: (sourceCode copyFrom: 1 to: bodyStart - 1) on: aFileStream] ifFalse: [aFileStream nextPutAll: '\begin{method}'; lf; tab; nextPutAll: '\upArrow self'; lf; nextPutAll: '\end{method}'; lf. ^self]. numberOfCharactersOnThisLine _ 0. (sourceCode copyFrom: bodyStart + 1 to: sourceCode size) do: [:char | numberOfCharactersOnThisLine _ numberOfCharactersOnThisLine + 1. (numberOfCharactersOnThisLine > 80 and: [char asInteger <= Character space asInteger]) ifTrue: [aFileStream lf. numberOfCharactersOnThisLine _ 0]. (CharacterMappingDictionary includesKey: char) ifTrue: [aFileStream nextPutAll: (CharacterMappingDictionary at: char). char = Character cr ifTrue: [aFileStream lf. numberOfCharactersOnThisLine _ 0]] ifFalse: [aFileStream nextPut: char]]. (sourceCode at: sourceCode size) ~= Character cr ifTrue: [aFileStream lf]. aFileStream nextPutAll: '\end{method}'; lf! printOutOn: aFileStream "print me out on aFileStream" self printOutDefinitionOn: aFileStream. self printOutCommentOn: aFileStream. self organization categories do: [:heading | self printOutProtocol: heading on: aFileStream].! printOutStartUp: fileStream fileStream nextPutAll: '\documentstyle{article}';lf. fileStream nextPutAll: '\input{a4l}';lf. fileStream nextPutAll: '\input st80Macros ';lf. fileStream nextPutAll: '\begin{document}';lf. self initializeLatexCharacterMappingDictionary! printOutTimeStamp: aStream with: aString | dateTime | dateTime _ Time dateAndTimeNow. aStream nextPutAll: '\timeTitle{', (dateTime at: 1) printString, ' at ', (dateTime at: 2) printString, '\ \ \ \bf ', aString, '}' ; lf! ! !SystemOrganizer methodsFor: 'fileIn/Out'! printOutCategory: category | aFileStream | Cursor tex showWhile: [Transcript refresh; cr; cr; show: 'Printing out category: ' , category. aFileStream _ FileStream fileNamed: (category , '.tex'). Object printOutStartUp: aFileStream. Object printOutTimeStamp: aFileStream with: category. self printOutCategory: category on: aFileStream. Object printOutCloseDown: aFileStream. aFileStream shorten; close]! printOutCategory: category on: aFileStream | class first | first _ true. (self superclassOrder: category) do: [:class | first ifTrue: [first _ false] ifFalse: [class printOutMacro: '\classSeparator' with: nil on: aFileStream]. class printOutOn: aFileStream. class class printOutOn: aFileStream]! ! !FileDirectory class methodsFor: 'utilities'! fixFileName: aFileName "Make the file name a valid file name." ^((aFileName copyReplaceAll: ' ' with: '_') copyReplaceAll: '*' with: '%') copyReplaceAll: ':' with: '='! ! ' sent: r6 goodies 2/2/88 Headings, order of printout, bugs in comments, etc improved 15/7/88.